home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / prlgbnc1.lha / Bench / meta_qsort.pl < prev    next >
Text File  |  1990-06-22  |  3KB  |  103 lines

  1. % generated: 8 March 1990
  2. % option(s): 
  3. %
  4. %   meta_qsort
  5. %
  6. %   Ralph M. Haygood
  7. %
  8. %   meta-interpret Warren benchmark qsort
  9. %
  10. % For any meta-variable ~X~, interpret(~X~) behaves as if
  11. %   
  12. %  interpret(~X~) :- ~X~.
  13. %  
  14. %  Thus, for example, interpret((foo(X), bar(X), !)) behaves as if
  15. %  
  16. %  interpret((foo(X), bar(X), !)) :- foo(X), bar(X), !.
  17. %  
  18. %  Note that though ~X~ may contain cuts, those cuts cannot escape from
  19. %  interpret(~X~) to effect the parent goal; interpret(!) is equivalent
  20. %  to true.
  21. %  
  22. %  Cuts inside ~X~ are executed according to the rule that conjunction,
  23. %  disjunction, and if-then-else are transparent to cuts, and any other
  24. %  form is transparent to cuts if and only if it can be macro-expanded
  25. %  into a form involving only these three without interpret/1.  If-then
  26. %  and negation are the only such other forms currently recognized; ( A
  27. %  -> B) is equivalent to ( A -> B ; fail ), and \+ A is equivalent to
  28. %  ( A -> fail ; true ).
  29.  
  30. meta_qsort :- interpret(qsort).
  31.  
  32. interpret(Goal) :-
  33.     interpret(Goal, Rest),
  34.     ( nonvar(Rest), !,
  35.       interpret(Rest) 
  36.     ; true 
  37.     ).
  38.  
  39. interpret(G, _) :-
  40.     var(G), !,
  41.     fail.
  42. interpret((A, B), Rest) :- !,
  43.     interpret(A, Rest0),
  44.     ( nonvar(Rest0) ->
  45.         Rest = (Rest0, B)
  46.     ; interpret(B, Rest)
  47.     ).
  48. interpret((A ; B), Rest) :- !,
  49.     interpret_disjunction(A, B, Rest).
  50. interpret((A -> B), Rest) :- !,
  51.     interpret_disjunction((A -> B), fail, Rest).
  52. interpret(\+A, Rest) :- !,
  53.     interpret_disjunction((A -> fail), true, Rest).
  54. interpret(!, true) :- !.
  55. interpret(G, _) :-
  56.     number(G), !,
  57.     fail.
  58. interpret(G, _) :-
  59.     is_built_in(G), !,
  60.     interpret_built_in(G).
  61. interpret(G, _) :-
  62.     define(G, Body),
  63.     interpret(Body).
  64.  
  65. interpret_disjunction((A -> B), _, Rest) :-
  66.     interpret(A, Rest0), !,
  67.     ( nonvar(Rest0) ->
  68.         Rest = (Rest0 -> B)
  69.     ; interpret(B, Rest)
  70.     ).
  71. interpret_disjunction((_ -> _), C, Rest) :- !,
  72.     interpret(C, Rest).
  73. interpret_disjunction(A, _, Rest) :-
  74.     interpret(A, Rest).
  75. interpret_disjunction(_, B, Rest) :-
  76.     interpret(B, Rest).
  77.  
  78. is_built_in(true).
  79. is_built_in(_=<_).
  80.  
  81. interpret_built_in(true).
  82. interpret_built_in(X=<Y) :- X =< Y.
  83.  
  84. define(qsort,(
  85.        qsort([27,74,17,33,94,18,46,83,65, 2,
  86.               32,53,28,85,99,47,28,82, 6,11,
  87.               55,29,39,81,90,37,10, 0,66,51,
  88.                7,21,85,27,31,63,75, 4,95,99,
  89.               11,28,61,74,18,92,40,53,59, 8],_,[]))).
  90.  
  91. define(qsort([X|L],R,R0),(
  92.        partition(L,X,L1,L2),
  93.        qsort(L2,R1,R0),
  94.        qsort(L1,R,[X|R1]))).
  95. define(qsort([],R,R),true).
  96.  
  97. define(partition([X|L],Y,[X|L1],L2),(
  98.        X=<Y,!,
  99.        partition(L,Y,L1,L2))).
  100. define(partition([X|L],Y,L1,[X|L2]),(
  101.        partition(L,Y,L1,L2))).
  102. define(partition([],_,[],[]),true).
  103.